MorphologicalProperties.f90 Source File

Manage morphological properties



Source Code

!! Manage morphological properties
!|author:  <a href="mailto:giovanni.ravazzani@polimi.it">Giovanni Ravazzani</a>
! license: <a href="http://www.gnu.org/licenses/">GPL</a>
!    
!### History
!
! current version  1.1 - 22nd April 2024   
!
! | version  |  date       |  comment |
! |----------|-------------|----------|
! | 1.0      | 22/Nov/2022 | Original code |
! | 1.1      | 22/Apr/2024 | Flow direction convention set by user | 
!
!### License  
! license: GNU GPL <http://www.gnu.org/licenses/>
!
!### Module Description 
! Module to manage morphological properties
!
MODULE MorphologicalProperties

! Modules used: 

USE DataTypeSizes, ONLY: &
    !Imported type definitions:
    short, &
    long, &
    float 

USE LogLib, ONLY: &
    ! Imported routines:
    Catch

USE IniLib, ONLY : &
    !Imported types:
    IniList, &
    !Imported routines:
    IniOpen, &
    SectionIsPresent, &
    IniClose, &
    KeyIsPresent, &
    IniReadReal, &
    IniReadInt, &
    IniReadString
 
USE GridLib, ONLY: &
    !Imported type definitions:
    grid_integer, &
    grid_real, &
    !Imported routines:
    GridDestroy, &
    NewGrid

USE GridOperations, ONLY: &
    !Imported routines
    GridByIni, &
    CRSisEqual

USE RiverDrainage, ONLY : &
    !imported routines
    BuildReachNetwork, &
    !imported definitions:
    ReachNetwork

USE Morphology, ONLY : &
    !Imported rutines:
    SetFlowDirectionConvention
    

IMPLICIT NONE

!Global declarations:

TYPE (grid_real)    :: dem !!digital elevation model
TYPE (grid_integer) :: flowDirection  !! flow direction (ESRI convention)
TYPE (grid_integer) :: flowAccumulation  !! flow accumulation (number of cells)

TYPE (ReachNetwork) :: streamNetwork

LOGICAL   :: dem_loaded = .FALSE.
LOGICAL   :: flowDirection_loaded = .FALSE.
LOGICAL   :: flowAccumulation_loaded = .FALSE.
LOGICAL   :: streamNetworkCreated = .FALSE.

!Public routines
PUBLIC :: MorphologyInit

!Local (i.e. private) declarations 
TYPE (IniList), PRIVATE :: iniDB


!Local routines
type (grid_integer) :: horton

!=======
CONTAINS
!=======
! Define procedures contained in this module.


!==============================================================================
!| Description:
!   Initialize morphological properties
SUBROUTINE MorphologyInit &
!
( inifile, mask )

IMPLICIT NONE

! arguments with intent(in).
CHARACTER (LEN = *), INTENT(IN) :: inifile  !!name of configuration file
TYPE (grid_integer), INTENT(IN) :: mask !!domain analysis

! local declarations
REAL (KIND = float) :: maxReachLength  !!max length of a reach (m)
REAL (KIND = float) :: slopeCorrection !! slope value to correct negative values
TYPE (grid_integer) :: fdir !!overlay of flowdirection on mask
INTEGER (KIND = short) :: reachFileExport !!export reach list to file
INTEGER (KIND = short) :: reachShpExport !!export shape file of reach network
CHARACTER (LEN = 100) :: string
INTEGER (KIND = short) :: i,j

!-------------------------end of declarations----------------------------------

!open and load configuration file
CALL IniOpen (inifile, iniDB)

!read dem
IF (SectionIsPresent('dem', iniDB)) THEN
  CALL GridByIni (iniDB, dem, section = 'dem')
  IF  ( .NOT. CRSisEqual (mask = mask, grid = dem, checkCells = .TRUE.) ) THEN
       CALL Catch ('error', 'MorphologicalProperties',   &
			    'wrong spatial reference in digital elevation model' )
  END IF
  dem_loaded = .TRUE.
END IF

!flow direction
IF (SectionIsPresent('flow-direction', iniDB)) THEN
  CALL GridByIni (iniDB, flowDirection, section = 'flow-direction')
  !set flow direction convention
  IF (KeyIsPresent('flow-direction-convention', iniDB, section = 'flow-direction' )) THEN
     string = IniReadString ('flow-direction-convention', iniDB, section = 'flow-direction' )
     CALL SetFlowDirectionConvention (string)
  ELSE
      CALL Catch ('error', 'MorphologicalProperties',   &
			     'flow-direction-convention missing in section flow-direction ' )
  END IF
 
  IF  ( .NOT. CRSisEqual (mask = mask, grid = flowDirection, checkCells = .TRUE.) ) THEN
     CALL Catch ('error', 'MorphologicalProperties',   &
			     'wrong spatial reference in flow direction' )
  END IF
  flowDirection_loaded = .TRUE.
END IF


!flow accumulation
IF (SectionIsPresent('flow-accumulation', iniDB)) THEN
  CALL GridByIni (iniDB, flowAccumulation, section = 'flow-accumulation')
  IF  ( .NOT. CRSisEqual (mask = mask, grid = flowAccumulation, checkCells = .TRUE.) ) THEN
     CALL Catch ('error', 'MorphologicalProperties',   &
			     'wrong spatial reference in flow accumulation' )
  END IF
  flowAccumulation_loaded = .TRUE.
END IF


!stream network
IF ( SectionIsPresent ('stream-network', iniDB) ) THEN
    
   IF ( KeyIsPresent ('max-reach-length', iniDB, 'stream-network') ) THEN
       maxReachLength = IniReadReal ('max-reach-length', iniDB, 'stream-network')
   ELSE
       maxReachLength = - 1.
   ENDIF
   
   IF ( KeyIsPresent ('negative-slope-correction', iniDB, 'stream-network') ) THEN
       slopeCorrection = IniReadReal ('negative-slope-correction', iniDB, 'stream-network')
   ELSE
       slopeCorrection = - 1.
   ENDIF
   
   IF ( KeyIsPresent ('file-export', iniDB, 'stream-network') ) THEN
       reachFileExport = IniReadInt ('file-export', iniDB, 'stream-network')
   ELSE
       reachFileExport = - 1.
   ENDIF
   
   IF ( KeyIsPresent ('shp-export', iniDB, 'stream-network') ) THEN
       reachShpExport = IniReadInt ('shp-export', iniDB, 'stream-network')
   ELSE
       reachShpExport = - 1.
   ENDIF
   
   !create temporary flow direction grid 
   CALL NewGrid (fdir, mask, 0)
   
   !mask overlay
   DO i = 1, mask % idim
       DO j = 1, mask % jdim
           IF ( mask % mat (i,j) /= mask % nodata ) THEN
               fdir % mat (i,j) = flowDirection % mat (i,j)
           END IF
       END DO
   END DO
   
   
   CALL BuildReachNetwork (maxReachLength, slopeCorrection, fdir, &
                          flowAccumulation, dem, reachFileExport, &
                          reachShpExport, streamNetwork )
   
   !destroy fdir
   CALL GridDestroy (fdir)
   
   streamNetworkCreated = .TRUE.
   
END IF


!close ini
CALL IniClose (iniDB)

RETURN
END SUBROUTINE MorphologyInit


END MODULE MorphologicalProperties